FAO56PenmanMonteith Subroutine

private subroutine FAO56PenmanMonteith(airTemp, netRad, netRadFAO, rh, wind, fc, elevation, zws, zrhum, lai, pt, pe, pet)

Compute potential evapotranspiration with FAO56 Penman-Monteith model for a reference grass "A hypothetical reference crop with an assumed crop height of 0.12 m, a fixed surface resistance of 70 s m-1 and an albedo of 0.23."

References:

Allen, R.G.; Pereira, L.S.; Raes, D.; Smith, M. Crop Evapotranspiration-Guidelines for Computing Crop Water Requirements-FAO Irrigation and Drainage Paper 56, 9th ed.; Food and Agriculture Organization of the United Nations: Rome, Italy, 1998; ISBN 92-5-104219-5.

Lincoln Zotarelli, Michael D. Dukes, Consuelo C. Romero, Kati W. Migliaccio, and Kelly T. Morgan, Step by Step Calculation of the Penman-Monteith Evapotranspiration (FAO-56 Method), Agricultural and Biological Engineering Department, University of Florida, 2009. https://edis.ifas.ufl.edu/pdf/AE/AE45900.pdf

https://wetlandscapes.github.io/blog/blog/penman-monteith-and-priestley-taylor/

Arguments

Type IntentOptional Attributes Name
real(kind=float), intent(in) :: airTemp

air temperature [°C]

real(kind=float), intent(in) :: netRad

net radiation [W/m2]

real(kind=float), intent(in) :: netRadFAO

net radiation for reference vegetation, with albedo = 0.23 [W/m2]

real(kind=float), intent(in) :: rh

air relative humidity [0-100]

real(kind=float), intent(in) :: wind

wind speed [m/s]

real(kind=float), intent(in) :: fc

fractional coverage by vegetation [0-1]

real(kind=float), intent(in) :: elevation

terrain elevation [m a.s.l.]

real(kind=float), intent(in) :: zws

wind speed measurement heigth [m]

real(kind=float), intent(in) :: zrhum

relative humidity measurement heigth [m]

real(kind=float), intent(in) :: lai

leaf area index [m2/m2]

real(kind=float), intent(out) :: pt

potential transpiration (from vegetation) [m/s]

real(kind=float), intent(out) :: pe

potential evaporation (from water or saturated soil) [m/s]

real(kind=float), intent(out) :: pet

potential evapotranspiration [m/s]


Variables

Type Visibility Attributes Name Initial
real(kind=float), public, parameter :: R1 = 0.287

gas specific constant (kJkg^-1K^-1)

real(kind=float), public :: Tkv

virtual air temperature (K)

real(kind=float), public :: airPress

air pressure [KPa]

real(kind=float), public :: cp

humid air specific heat (MJkg^-1°C^-1)

real(kind=float), public :: des

the slope of the relationship between saturation vapour pressure and temperature

real(kind=float), public :: ea

actual vapor pressure (Pa)

real(kind=float), public, parameter :: epsilon = 0.622
real(kind=float), public :: es

saturation vapor pressure (Pa)

real(kind=float), public :: gamma

psychrometric constant [kPa °C-1]

real(kind=float), public :: groundHeat

ground heat flux [MJ m-2 s-1]

real(kind=float), public, parameter :: k = 0.41

von Karman’s constant

real(kind=float), public, parameter :: lambda = 2.453
real(kind=float), public :: netRadFAO_MJ

FAO net radiation in MJm^-2s^-1

real(kind=float), public :: netRadMJ

net radiation in MJm^-2s^-1

real(kind=float), public :: rabs

aerodynamic resistance of bare soil (s/m)

real(kind=float), public :: rhoAir

air density (kgm^-3)

real(kind=float), public :: srmin = 70

minimum stomatal resistance of reference grass [s/m]

real(kind=float), public :: ws2m

wind speed at 2m (m/s)

real(kind=float), public :: z = 0.12

reference grass height [m]

real(kind=float), public :: z1

bare soil heigth (m)

real(kind=float), public :: zd1

bare soil zero plane displacement height (m)

real(kind=float), public :: zh1

relative humidity measurement heigth + z1 (m)

real(kind=float), public :: zm1

wind speed measurement heigth + z1 (m)

real(kind=float), public :: zrh1

Roughness length governing transfer of heat and vapor above zd1 (m)

real(kind=float), public :: zrw1

Roughness length governing momentum transfer (m)


Source Code

SUBROUTINE FAO56PenmanMonteith &
!
(airTemp, netRad, netRadFAO, rh, wind, fc, elevation, zws, zrhum, lai, pt, pe, pet)

IMPLICIT NONE

!Arguments with intent(in):
REAL (KIND = float), INTENT(in)  :: airTemp !!air temperature [°C]
REAL (KIND = float), INTENT(in)  :: netRad !! net radiation [W/m2]
REAL (KIND = float), INTENT(in)  :: netRadFAO !! net radiation for reference vegetation, with albedo = 0.23 [W/m2]
REAL (KIND = float), INTENT(in)  :: rh !! air relative humidity [0-100]
REAL (KIND = float), INTENT(in)  :: wind !! wind speed [m/s]
REAL (KIND = float), INTENT(in)  :: fc !! fractional coverage by vegetation [0-1]

REAL (KIND = float), INTENT(in)  :: elevation !! terrain elevation [m a.s.l.]
REAL (KIND = float), INTENT(in)  :: zws !! wind speed measurement heigth [m]
REAL (KIND = float), INTENT(in)  :: zrhum !! relative humidity measurement heigth [m]
REAL (KIND = float), INTENT(in)  :: lai !! leaf area index [m2/m2]


!Arguments with intent(out):
REAL (KIND = float), INTENT(out) :: pt		!! potential transpiration (from vegetation) [m/s]
REAL (KIND = float), INTENT(out) :: pe		!! potential evaporation (from water or saturated soil) [m/s]
REAL (KIND = float), INTENT(out) :: pet		!! potential evapotranspiration [m/s]

!local declarations:
REAL (KIND = float) :: z = 0.12 !! reference grass  height [m]
REAL (KIND = float) :: srmin = 70 !! minimum stomatal resistance of reference grass [s/m]

REAL (KIND = float) :: groundHeat !!ground heat flux [MJ m-2 s-1]
REAL (KIND = float) :: es !!saturation vapor pressure (Pa)
REAL (KIND = float) :: ea !!actual vapor pressure (Pa)
REAL (KIND = float) :: des !!the slope of the relationship between saturation vapour pressure and temperature
REAL (KIND = float) :: airPress !!air pressure [KPa]
REAL (KIND = float) :: gamma !!psychrometric constant [kPa °C-1]
REAL (KIND = float) :: ws2m !!wind speed at 2m (m/s)
REAL (KIND = float) :: z1  !!bare soil heigth (m)
REAL (KIND = float) :: zm1  !! wind speed measurement heigth + z1 (m)
REAL (KIND = float) :: zh1  !! relative humidity measurement heigth + z1 (m)
REAL (KIND = float) :: zd1   !! bare soil zero plane displacement height (m)
REAL (KIND = float) :: zrw1  !! Roughness length governing momentum transfer (m)
REAL (KIND = float) :: zrh1   !! Roughness length governing transfer of heat and vapor above zd1 (m)
REAL (KIND = float) :: rabs !! aerodynamic resistance of bare soil (s/m)
REAL (KIND = float) :: cp !!  humid air specific heat (MJkg^-1°C^-1)
REAL (KIND = float) :: Tkv  !! virtual air temperature (K)
REAL (KIND = float) :: rhoAir !!air density (kgm^-3)
REAL (KIND = float) :: netRadMJ !! net radiation in MJm^-2s^-1
REAL (KIND = float) :: netRadFAO_MJ !! FAO net radiation in MJm^-2s^-1
REAL (KIND = float), PARAMETER :: k = 0.41 !!von Karman’s constant
REAL (KIND = float), PARAMETER :: epsilon = 0.622   ! ratio molecular weight of water vapour/dry air
REAL (KIND = float), PARAMETER :: lambda = 2.453 !2.2647 !!latent heat of vaporization (MJ / kg)
REAL (KIND = float), PARAMETER :: R1 = 0.287	!!gas specific constant	(kJkg^-1K^-1)
!-----------------------------------------end of declarations------------------

! compute saturation vapor pressure
es = 0.6108 * EXP ( ( 17.27 * airTemp ) / ( airTemp + 237.3 ) )

!actual vapor pressure
ea = rh / 100. * es

!compute the slope of saturation vapour pressure curve (Allen. et al. 1998)
des = ( 4098. * es ) / ( ( airTemp + 237.3 )**2. )

!compute atmospheric pressure
airPress = 101.3 * ( ( 293. - 0.0065 * elevation ) / 293. )** 5.26

!compute psychrometric constant
gamma = 0.665 * 0.001 * airPress


!move wind speed to 2 m reference height (Zotarelli et al., 2009)
IF ( zws /= 2. ) THEN
	ws2m = wind
ELSE
	ws2m = wind * 4.87 / LOG ( 67.8 * zws - 5.42 )
END IF

!aerodynamic variables of bare soil
z1 = 0.1 
zm1 = zws + z1
zd1 = 2. / 3. * z1
zrw1 = 0.123 * z1
zh1 = zrhum + z1
zrh1 = 0.1 * zrw1

!compute aerodynamic resistance of bare soil
rabs = LOG ( (zm1 - zd1) / zrw1 ) * LOG ( (zh1 - zd1) / zrh1 ) / ( k**2 * wind ) 

! humid air specific heat (MJkg^-1°C^-1)
cp = gamma * epsilon * lambda / airPress

!virtual air temperature (K)
Tkv = 1.01 * ( airTemp + 273. )

!air density (kgm^-3)
rhoAir = airPress / ( Tkv * R1 )


!check and convert net radiation
IF ( netRad < 0 ) THEN
	netRadMJ = 0.
ELSE
	netRadMJ = netRad * 0.000001
END IF 

IF ( netRadFAO < 0 ) THEN
	netRadFAO_MJ = 0.
ELSE
	netRadFAO_MJ = netRadFAO * 0.000001
END IF 

! compute ground heat flux as a fraction of net radiation Anderson et al. (2007)
! groundHeat is assumed to affect evaporation from bare soil only
groundHeat = 0.31 * netRadMJ

!compute evaporation (from saturated bare soil or water)
    
pe = ( des * ( netRadMJ - groundHeat ) + rhoAir * cp * ( es - ea ) / rabs  )  / &
     ( lambda *  ( des + gamma )  ) * millimeter
    

!compute transpiration from vegetation
IF (fc > 0.) THEN  

    pt =  ( 0.408 * des * ( netRadMJ - groundHeat ) + gamma *  (900. / day ) / &
          ( airTemp + 273. ) * ws2m * (es - ea) ) / &
          (des + gamma * ( 1. + 0.34 * ws2m ) ) * millimeter

ELSE
    
    pt = 0.

END IF

!compute evapotranspiration

pet = ( 1. - fc) * pe + fc * pt

RETURN
END SUBROUTINE FAO56PenmanMonteith